perm filename HALNEW.DOC[HAL,HE] blob sn#128395 filedate 1974-10-31 generic text, type C, neo UTF8
COMMENT ⊗   VALID 00011 PAGES
C REC  PAGE   DESCRIPTION
C00001 00001
C00002 00002	Yet another document.  Ideas for changes to current syntax,
C00006 00003	COMPILE-TIME VARIABLES
C00019 00004	TOB -- more on data types
C00027 00005	Yet more on dimensions & units.
C00036 00006	A few thoughts on rotations. 
C00044 00007	A bit more on rotations -- derivation of rotation matrix.
C00047 00008	Yet more on rotations -- axis-magn form from rot matrix
C00050 00009	Labels, statement naming, task begin, etc.
C00053 00010	ODDS & ENDS
C00059 00011	Suggested names for "HAL"
C00062 ENDMK
C⊗;
Yet another document.  Ideas for changes to current syntax,
semantics, abilities of HAL.  For discussion at meetings and eventual
inclusion into the memo.

UNITS
	There are two problems associated with units: 1)What do you
do about conflicting uses of datatypes (scalar both distance and
time), and 2)within one use (say distance), how do you determine what
measurement scheme is being used (centimeters or inches)? A tertiary
problem is 3)whether any eventual scheme should allow different
conventions within different blocks, and whether Algol scope rules
are to be observed, and how.
	The first point leads one to posit that any conversion of
scalars should be done at the point of use, not the point of
acquiring a value. But then if units follow scope rules, the same
scalar can be understood to refer to, say, seconds in one block and
jiffies in an innermore block.  This can lead to programming errors.
	Several alternatives suggest themselves: A)Dispense with
UNITS and demand that standard scalar units are centimeters, seconds,
kilograms.  B)Same as A but allow overriding statements at
point-of-use, so that the programmer can refer to X JIFFIES.  C)Same
as B but make the specification look like a function call:
JIFFIES(X).  Unfortunately, the correct use of this is
counterintuitive.  D)Allow a UNITS statement which has algol scope
which causes a point-of-use conversion for each scalar use.  E)Create
new datatypes: SCALAR, TIME, DISTANCE, MASS, each one having a
default measuring scheme.  This prevents multiple erroneous use of
scalars and provides consistency checks. F)Keep one type of scalar,
but propagate dimensions during arithmetic. Scalar constants would
have the word SECONDS, KILOS, CENTIMETERS attached.  Arithmetic would
check for consistancy: seconds cannot be added to kilos, but if they
are multiplies, one gets second-kilos. This adds the need to keep a
canonical list structure for dimensions along with all scalars.
	The problem is compounded for vectors.  Certainly we do not
want one coordinate of a vector to have dimension different from
another.  It also seems that we only want vectors of type distance;
time vectors are meaningless.  But we are also using vectors to
represent rotations.  This can lead to serious misunderstandings, I
think.  The only currently safe solution is to apply the conversion
from vector to rotation-transform at the time of application, never
at the time of value assignment.
COMPILE-TIME VARIABLES

	If CTVs are allowed to take on arbitrary character strings as
values, then parsing is impossible, since the parser has no idea what
to do with the CTV when it is evaluated.
	If CTVs are restricted to only take on expressions as values,
then these desiderata are missing: 1)To be able to write a library
routine which can have code supplied at the point of call instead of
at the point of writing.  Expressions are not powerful enough to
express arbitrary statements.  2) To be able to pass as arguments to
library routines complicated data, such as code (already mentioned)
and world-knowledge which is in the form of asserted patterns, not
variable values.
	Part of the problem can be alleviated by allowing COMPILE IF
to appear where a statement, clause, or expression is needed.
Currently, it is only allowed in place of a statement or expression.
I think that the extension to clauses should be made on general
principles. It is quite possible that we also want regular IF to take
clauses as their scope, although this can lead to uncompilable
constructs like
	MOVE YELLOW
		IF cond1 THEN TO YPARK ELSE TO ⊗;

	This solution does not treat the case where the writer of the
library routine has no idea what tests need be done during a move, so
cannot even put in the skeleton test and surround it in COMPILE IFs.
I seriously doubt we want that sort of flexibility, but if we do,
then we are forced to allow CTVs to take on any language construct of
the form statement, clause, or expression.  Some typing may well be
necessary to distinguish one type of clause from another, so that the
parser can check that a move has exactly one destination, for
example.  If we want the parser to be a bit more stupid, perhaps we
can leave off the typing.  What remains is that the internal
structures generated by the parser have to have a standard form
(which they currently do not) for all clauses.  That might not be so
bad an idea, at that; it would bring out the clause nature of the
language a bit better.  It would also require that each clause header
be an unambiguously reserved word, so that the parser could tell how
to parse the clause out of context, in the case that a clause is
assigned as the value of a CTV.  (Might as well have the parser parse
it as soon as it sees it, not defer evaluation.) 
	I think it would be a bad idea to have to declare the types
of CTVs; they are intended to be amorphous (just as are scalars.
There are similarities bewteen this discussion and the one on UNITS
on the previous page.).  Another option, necessary in the case of
deferred evaluation (read parsing), would be to specify the type of
the CTV at the point of use. This is acceptable from a language
design point of view, but can be very wearisome on the programmer,
since it is to be expected that a CTV will be used much more often
than it will be declared.

RHT -- I'm really too tired to go into much detail right now on this.
The problem seems to be (primarily) a parsing and "well structured-ness"
problem.  If we only have a few meta-types allowed (STATEMENT, EXPRESSION,
ATOM, & (perhaps) CLAUSE), I would be for declaring the types explicitly.
Thus:

	STATEMENT s1,s2;
	EXPRESSION e;

	s1← ⊂ MOVE YELLOW TO ⊗ ... ⊃  {or some such}

	:

	#(s1)

Also, perhaps we should give some thought to allowing (at least) expressions
to be runtime variables, too.  Does that get us in trouble??  If we 
allow em, then the declaration might want to look like

	COMPILE EXPRESSION e;

Also, we will still most likely need a way to establish parser context
for the "constants" that go into these beasts.  

I kind of liked the stuff we said at the meeting about CLAUSEs but am
still a bit troubled over what might happen to the HAL intermediate forms.
(One solution may be to have a special bucket in each semantics record for 
unresolved clause variables, but that seems like a kluge).  

RF -- I am agreeable to the datatypes STATEMENT, EXPRESSION, CLAUSE,
ATOM, PATTERN.

	While I am on the subject, I recommend that ATOMs be declared
before they can be used as parts of patterns.  This will prevent
spelling errors from causing obscure bugs. Unfortunately, this will
cause a confusion between ATOMVARS and ATOMS.

RHT -- 3 questions: (1) I'm a bit uncertain about the use for pattern
variables.  (2) Do we need ATOMVARS?? My understanding was that an ATOM would be
a variable that could only take other variable names as a value.  I agree with
Ray about requiring that any identifier in a pattern be declared beforehand.
Seems like a very good idea.  Presumably, the atoms required for standard
templates will all be pre-declared.  There is one small difficulty: declarations
follow block structure, but the database endures forever.
Does this matter? Can it ever cause difficulties?
(3) What do people think about runtime data types  for expression, etc??

RF -- results of discussion with RHT, LOU 10/128/74.

1)  A generalized expression is defined as follows:
	a) The name of a declared identifier
	b) A constant
	c) A function applied to an expression
		i) The function # returns a constant when applied to a FRAME
		ii) The functin STATEMENT returns a statement
		iii) The function EXPR is a no-op
		iv) The function BIND returns an expression
	d) A function applied to a list of expressions (enclosed
	  in parentheses, separated by commas.
		i) The function PATTERN returns a pattern.
		ii) The function VECTOR returns a vector constant
		iii) The function TRANS returns a trans constant
	e) Two expressions separated by an infix operator.

2)  Preevaluation of an expression is defined as follows:
	a) The prevalue of a declared identifier is itself (no-op)
	b) The prevalue of a constant is itself (no-op)
	c) The prevalue of a function:  First, preevaluate each argument.
		i) The prevalue of #(ident) is the planning value of ident.
		ii) Prevalue of STATEMENT(...) is a statement
		iii) Prevalue of EXPR(junk) is junk
		iv) Prevalue of BIND is itself (no-op)
	d) Preevaluate each of the arguments.
	   If each is constant, can somethimes return a constant.
	e) Preevaluate each of the arguments.
	  If each is a constant, result is a constant.

3)  The following types are allowed in HAL:
	a) Algebraic:  SIMPLE, TIME, DISTANCE, MASS, <new scalar types>,
		VECTOR, ROTATION, TRANS, FRAME.  
	These have both compile-time and run-time values.
	b) ATOMS.  Take as planning values identifiers.  Can be
		declared restricted to SIMPLE ...FRAME.
		Sample declaration:  VECTOR ATOM VA1, VA2;
	c) CHUNKS.  Take as planning values algebraic constants,
		expressions, statements, clauses, patterns.
	  May be optionally typed:
		EXPRESSION CHUNK EP1; FRAME CHUNK PP1;

4)  The semantics of assignment arrow "←":
	a) Evaluate LHS to an identifier.
	b) Preevaluate RHS.
	c) Emit code for evaluation of RHS, assignment to LHS.
	d) Find planning value of RHS, update planning value of LHS.

5)  The semantics of planning assignment arrow "←←":
	a)  Evaluate LHS to an identifier.
	b)  Preevaluate RHS.
	c)  Update planning value of LHS to result of b).


6)  The "←" is only applicable to algebraic variables.
    The "←←" is applicable to all types.


7)  Examples:
FRAME F1;
ATOM ONTOP, UNDER, POSITION;
FRAME ATOM FA1;
EXPRESSION CHUNK EP1;


EP1 ←← F1→F1;
ASSERT PATTERN (F1, ONTOP, #(EP1));
FA1 ← F1;
POSITION ← ONTOP;
ASSERT PATTERN (#(FA1), #(POSITION), F1→F1);

The two assertions are equivalent, and both are different to:
ASSERT PATTERN (FA1, POSITION, #(EP1));
ASSERT PATTERN (#(FA1), #(POSITION), EP1);

8)  Construction primitives all have names.  Here are some of them:
VECTOR (3,2,4);
FRAME (V1, ROT1);
STATEMENT (FOR I ← 1 STEP 1 UNTIL 10 DO J ← J*I);
TOB -- more on data types

I would like to see user-defined data types.  For example:
	TIME T;
	INTEGER INDEX I;
This permits type checking, which is particularly useful for
subroutine calls.  It also permits dimension checking:
	VELOCITY (DISTANCE/TIME) V;

which would then be checked by expanding out the units of all variables
involved.  That would require only three numbers for each dimensional
variable, the exponent of the DISTANCE, MASS, TIME.
I propose this for discussion only.  How much does it complicate the
compiler.  Useful for debugging and clarity of code.  

RHT -- so long as we allow assignments only into variables with the
correct dimensionality, I think that all checking can be done in the
parser.  As an extra added bonus, if we ever want to go back to allowing
users to define units, this gives a very good hook.  It seems like a
"nice hack" that might help prevent numerous user bugs.

RF -- Explicit distinction between scalars, times, distances, masses,
and combinations thereof is not a bad idea; it will prevent a class
of stupid mistakes.  Let me try to present a coherent system of
such things here.  This is a revised scheme, due to comments by
RHT on the original one.

DECLARATIONS OF SCALAR VARIABLES
	SIMPLE A, B;
	TIME C, D;
	MASS E, F;
	DISTANCE G, H;
	ANGLE I, J;  {This one is of doubtful utility}

	expanded types:
	DIMENSION FORCE = MASS*DISTANCE/TIME↑2;
	DIMENSION VELOCITY = DISTANCE/TIME;

	FORCE K, L; 
	VELOCITY M, N;

TYPING OF SCALAR CONSTANTS
	3.2	   (simple)
	3.2*SEC
	3.2*KG
	3.2*CM
	5.99*DEG
	65*CM/SEC

	That is, the words SEC, KG, CM, DEG are reserved.  They may
be multiplied or divided by any scalar expression, with the sole
effect that they modify the type.  Note that C*SEC is of the type
TIME↑2.  Thus, these words should only be used in conjuction with
constants, not variables.
	Newly defined dimensions, like FORCE, can get units via
macro definitions:
	
	DEFINE NEWTONS = "KG * CM * 1000 / SEC↑2"
	DEFINE CPS = "CM / SEC"
	DEFINE INCHES = "2.54*CM"
	DEFINE FEET = "12*INCHES"
	DEFINE FPS = "FEET/SEC"

CONVERSIONS
	The only allowed implicit conversion is from SIMPLE to any other
type.  Using the declarations above,
	A ← 3.2
	C ← 5*SEC
	G ← M * C
	K ← 21
    are legal, but
	A ← C
	F ← G
    are not.

	Variables can be converted from one type to another by
use of the words GM, etc.  For example, the force K can be converted
to units of mass like this:
	K * SEC↑2 / CM


RESTRICTIONS
	The control variable of a FOR loop may be of any scalar type.
Vectors and planes may only be composed of scalars of type DISTANCE.
(The conversion convention allows SIMPLE scalars as well.) 
	Scalar arithmetic operators are restricted in the expected
manner: Addition and subtraction demand compatible arguments, and
return the same type.  Multiplication and division take any scalar
types as arguments, and return an apppropriate type.  It is quite
reasonable that an intermediate calculation will yield a type which
has not been declared.  This is fine as long as the user does not try
to assign it to any declared variable.  
	Exponentiation demands a simple second argument, and
exponentiates the types.  If the second argument is not an integer, I
guess that is fine.  But if it is not a constant, but rather a
variable, then all bets are off; I suggest the resulting type be
"undefined".
	The result of a scalar extraction operator is of type
DISTANCE if the extraction is from a vector, and can be of type ANGLE
if from a rotation.


	I think this can be made into a complete system which will have
advantages over our current scheme.  As RHT mentioned, almost all the
syntactic checking can be done in the parser.  By the time the parser
is finished, all that remains is simple scalars.  This scheme solves
both the problems mentioned in the page on UNITS -- using same variable
for two different sememes, and having the system of measurement change
suddenly in a new block.

RHT -- This looks pretty winning -- seems like a good
merger of ideas.  I'm still a bit troubled over angles (see next page).
What are the benefits to including them at all? (One possibility might
be documentation -- the parser can secretly say "simple" when it sees 
"angle")
Also, the restriction that vectors only be composed of DISTANCE elements
seems needlessly tight.  It seems to me to suffice (and to cost no more) to
require that all elements of a vector have the same dimensionality.
This would allow vectors of, e.g., force components.
One more thing -- It seems to me that our internal representation should
be pure cgs (ie, use GM instead of KG) or MKS.  We can, of course, provide
a set of predefined macros or units for expressing one system in terms of the other.
I don't understand the advantages in using a "mixed" system internally
(if there are any, perhaps someone could explain?).


On the next page, there is a comment on tradeoffs in the use of macros for 
defining units.

(⊗⊗⊗⊗⊗⊗ RHT -- Con'd on next page ⊗⊗⊗⊗⊗⊗)

Yet more on dimensions & units.

RHT -- I broke this into a new page because the other one was getting
very long.

RHT -- Some of these comments have been rendered moot by RF's modification
of what used to be on the previous page.  Generally, it seems that
the chief diference is now in the use of text macros, as opposed to
some parsed structure to express different units.  As nearly as I can tell
the principal advantage to using text macros here is that it avoids
the need for one more language construct -- which can be a significant advantage.
The advantages to using a parsed structure include: (1) it may be a
bit easier to do constant compression if we have special syntax for defining
units. (2) You get an extra bug check at the time of definition to
be sure that the defined units have the correct dimensions. 
(3)  You can perhaps supply a nicer looking print statement. (4) The
door is kept open for setting default typein modes, if we ever want them.
I don't have any very strong (or even medium strong) feelings on which
is better.  

RHT -- **** Note: It seems that RF & I now are both leaning very strongly
	towards having only one set of "built-in" units, and using macros
	to get other flavors. ****

The comments on angles are still current.

RHT -- A few comments.  I like the basic idea of all this, but have
some reservations:

(1) It seems much cleaner to use normal expression syntax in the
newtype stuff.  Thus:

	DIMENSION FORCE = MASS*DISTANCE/(TIME↑2);

(2) I don't see the need for all the types on scalars.  In any event,
i'm not very happy with the use of "TIME" to mean "SECONDS", as seems
to be the case here.  The point is that there really is a difference
between dimensions and units.  If we want units, then we should use
their proper names.  If we want, we can supply a few predefined
identifiers for CGS, MKS, & common English units.  Also, I'm not very
happy with the use of dimensional names as some sort of postfix
operators, since it seems that what is actually meant is an implied
multiplication.  There is a certain "readability" advantage in using
concatenation to mean multiplication of units, but I'm afraid this is
apt to cause trouble for the parser, and can make things fairly
confusing if complicated expressions are involved, whereas explicit
multiplications are pretty easy to understand and, somehow, don't
seem to involve as large a conceptual jump.

(3) I don't understand the reason for outlawing non-integer powers of
dimensions, since all we really need is to assure that the dimensions
are correct by the time a value is used in one of the language
statements.  For instance, the "deep water" wave velocity equation
may be written:

	c = q*sqrt(λ)

where 
	λ = wavelength
	q = sqrt(g/(2*π))
	g = accelation due to gravity.

One possible solution would be to introduce two new sorts of
declarations:

	DIMENSION <id> = <def> ;
	<dimension id> UNIT <id> = <def>;

where the <def>s are arithmetic expressions invloving previously
defined dimensions and units, respectively.  Thus we might have:

	DIMENSION FORCE = MASS*DISTANCE/(TIME↑2);
	DIMENSION ENERGY = FORCE*DISTANCE;

	FORCE UNIT DYNES = GRAM*CM/(SEC↑2);
	FORCE UNIT NEWTONS = KG*M/(SEC↑2);

In this scheme, all numbers remain dimensionless.  Thus, 

	FORCE UNIT NEWTONS = 100000*DYNES;
	DISTANCE UNIT INCHES = 2.54*CM;
	DISTANCE UNIT FEET = 12*INCHES;
	VELOCITY UNIT FPS = FEET/SEC;

As before, variables would be declared by giving their dimension
name.

	FORCE F1,F2,F3;
	TIME T;
	SIMPLE C;
	VELOCITY V;

All variable values would be stored internally in a "normal" set of
units. (perhaps CGS).  All unit conversions could be handled pretty
cleanly by the parser, which could substitute definitions back to the
root system of units, and then insert the appropriate conversion
factor.  For instance,

	ENERGY KE;
	:
	KE← 100*KG*(10*FPS)↑2 

Would eventually give 

	KE ← 100000*(304.8)↑*GRAM*CM↑2/SEC↑2;

Similarly, dimensions would be calculated when parsing the expresion
& checked when parsing the assignment statement.

In this scheme, the CONVERT function gets replaced by simple
multiplication.

I'm a bit troubled by the ANGLE dimension, which (somehow) doesn't
seem to have quite the same physical significance as the others. I
suppose part of the problem is that a function like 

	sin(x)

usually assumes that x is a dimensionless number.  Also, if you
consider the normal interpretation for various physical formulae,
angles are treated as dimensionless.  E.g.,

	<rotation energy> = <moment of inertia>*<rotation rate>↑2

should give energy units: (m*d↑2/t↑2), which contains no "angle"
term. In this scheme, a degree is merely the number π/180.  Such a
predefined constant is trivial to provide.

Thus, we might say something like

	SIMPLE x,y;
	:
	x←sin(π+y)+cos(100*degrees);

In any event, there is a fair amount of convenience to be gained if
angle represention used by the compiler should be based on
dimensionless numbers -- ie "radians" -- if for no other reason than
that that is what the SAIL arithmetic routines use.  

A few thoughts on rotations. 

RHT -- still very rough, but ...

Let's assume (for the moment anyhow) that we are going to add a data
type "rotation".  There seem to be a number of reasons for
representing rotations (in the runtime system) as matrices (whether
3*3, 3*2, or something else).  This representation isn't particularly
well suited for user input or as an internal form for many of the
world modelling and decision making parts of the compiler, although
it seems to be fine for the trajectory planning parts of the
compiler.  This suggests that we should find some simple input
form(s) and internal representation that can be used throughout the
early phases of the compilation process, and which can then be turned
into a transformation (or simple rotation) matrix for the benefit of
those modules (eg traj planner & runtime) that prefer such a form.

I suggest that the rules for rotation application follow those for 
transforms.  Ie.

	<rot>*<vect>  →→ <a rotated vector>
	<rot>*<rot>   →→ a rotation

	R1*R2*V = (R1*R2)*V = R1*(R2*V)

A number of different forms (for user input, anyhow) have been
suggested. One such scheme might look something like:

	∂(x=a,x'=b,z''=c) 

or perhaps

	∂(a*x,b*x',c*z'')

Here I've used ∂ to be a "rotate" operator.  Aside from syntax
problems, which are pretty ugly, the idea is that you rotate about
the named axes by the named amount, with a ' getting added to each
axis with each minor rotation operation.  This scheme has a number of
advantages (e.g. it is easy to see how a user could define a number of common
rotation conventions).  On the other hand, there are some drawbacks
that result from restricting the "primitive" rotations to occur about
coordinate axes.  E.g., to express a known rotation about an
arbitrary axis, the user either must derive an equivalent rotation in
his head or must insert additional "dummy" rotations to get the
desired axis aligned with a coordinate axis, rotate about it, and
then put the rotation axis away.  This can lead to confusing code,
and is especially bothersome for those parts of the compiler that
wish to work with degrees of freedom.  Finally, I'm not too sure that
BGB-style rotation conventions are very naturally expressed.  More
generally, it is only really "natural" for those schemes that express
rotations in terms of canonical axes.  Also, a fair amount of effort
is involved in parsing.

These problems are much diminished if we go ahead and allow rotations
about arbitrary axes.  For instance, we can compose rotations of
primitive elements like

	∂(axis,amount)

which says to rotate by the specified amount about the specified
axis.  This scheme has a number of advantages: (1) It seems fairly
"natural" as a way to think about rotations (e.g. it is easy to
visualize) (2) The basic element is somewhat simpler without giving
up a great deal of power. (3) This form is considerably easier for
the various world modelling & vhll primitives to "understand",
especially where degrees of freedom are involved.  (4) It subsumes
the other form, since, for instance,

	∂(z=α,x'=β)

could be expressed as

	∂( ∂(z,α)*x, β)*∂(z,α)

One disadvantage in giving up the "'" notation is that you wind up
typing a lot of characters to rotate the various axes.  This doesn't
seem too bad, however, since macros can hide the extra typing and
since the semantics of many rotations are such that the axis may be
specified directly. (Note, it may be possible to get the "'"s back
via some special syntactic structure, with the parser translating
into the more primitive internal form).

Frequently, the axis about which you wish to spin a body is more
conveniently expressed in terms of a pair of angles (which I'll call
"axtilt" and "axrot"):

	3angleform(axtilt,axrot,magn)
		=∂( ∂(z,axrot)*∂(y,axtilt)*z,magn)

I.e. "axtilt" is the angle the axis of rotation makes with the z
axis, and "axrot" is the angle the projection of the rotation axis
onto the x-y plane makes with the x-axis.  These three rotation
angles are especially convenient when modeling degrees of freedom
since the various constraints "decouple" nicely when expressed in
terms of these variables, and it is fairly easy to derive the
appropriate mathematical expressions from semantic information about
the objects.

If we adopt some sort of "rotation about specified axis" scheme, then
it may prove very convenient for many parts of the compiler to use
this two-angle form to represent the axis (internally, at least). If
this turns out to be the case, then it should be an easy matter to
reconvert to whatever form the trajectory calculators desire.
A bit more on rotations -- derivation of rotation matrix.

Given an axis  r=(r[x],r[y],r[z]) and an angle w, we want
the rotation matrix R that corresponds to a rotation of w
about r. (note: r[x] means the x-component of r, i.e., r.x)

One easy way to compute this is via 

	R = inv(A)*B*A

where A is any rotation matrix such that

	A*r=z

and B represents a rotation of w about the z axis.  I.e.

		(cos(w)	 sin(w)	0)
	B =	(-sin(w) cos(w)	0)
		( 0	 0	1)

There are three cases:

case 1: r=z, then A=I works fine, and

	R=B

Case 2: r=-z, Then 

	R=B(-w)

case 3:	The rest; i.e., r[x]↑2+r[y]↑2≠0.
Actually, it will be easier to find inv(A).  I.e., some C such that

	r=C*z

Let

	v=(1/(r[x]↑2+r[y]↑2))*(-r[y],r[x],0)

Note that 
	v . r = 0
	v cross r = a unit vector orthog to v & r.
	In fact, v cross r, v, and r form a RH coord system.

Then 

	C = (v cross r,v,r)

will be a rotation.  Now,

	inv(A)=C
	A=inv(C)=transpose(C)

Therefore, 

	R = C*B*transpose(C)

One possible refinement of this method is to pick an axis qε(x,y,z) that
minimizes q[r].  & then pick B & C to give

	B = rotation of w about axis q
	r = C*q

	R = C*B*transpose(C)

This has the advantage of keeping the scale factor used to make v a reasonable
number, and, hence, avoids numerical degeneracies.
Yet more on rotations -- axis-magn form from rot matrix

Given rotation matrix R, you want to find the axis vector
r ( |r|=1) such that Rr=r. & the rotation magnitude w.  (Actually,
there will be two such axes, with 

	r1 = - r2
	w1 = - w2

To do this, note that any vector v will have 

	(Rv-v).r = 0

I.e., Rv-v will be perpendicular to r.  
Therefore, we can find the axis r via the following algorithm:

1. form  x'=Rx-x,  y'=Ry-y. If x'=0 then r=x; if y'=0 then r=y.
Otherwise, go on to step 2.  (Note, if desired, can also check
for z'=0.  Also note that Rx is just the first column of R, etc.)

2. r = cross(x',y')/|cross(x',y')|

*********************************************
A nice result for constraints:

It is frequently convenient to express constraints on allowable values for
some orientation vector b by means of 

	v.b ? λ		

where ? is some relation, v is a (unit) vector, and λ is a scalar.
If the vector b can be rotated by some rotation R(r,w) this turns into

	transpose(v)*R*b ? λ

where we have expressed everything in terms of matrix products.
Using R=C*B*inv(C), we can rewrite this 

	trans(v)*C*B*inv(C) ? λ

Since 
	trans(v)*C = trans(trans(C)*v)
		   = trans(inv(C)*v)

We can rewrite this  as

		  [ cos(w) -sin(w)  0]
	trans(v')*[ sin(w)  cos(w)  0]*b' ? λ
		  [  0       0      1]

where

	v'=inv(C)*v  b'=inv(C)*b

This gives us

	Q1*cos(w)+Q2*sin(w) ? Q3

where 

	Q1 = b'[1]*v'[1]+b'[2]*v'[2]
	Q2 = b'[1]*v'[2]-b'[2]*v'[1]
	Q3 = λ-b'[3]*v'[3]

If we now set

	sin(β)= Q1/sqrt(Q1↑2+Q2↑2)
	cos(β)= Q2/sqrt(Q1↑2+Q2↑2)
	α= Q3/sqrt(Q1↑2+Q2↑2)

We get 

	sin(β)*cos(w)+cos(β)*sin(w) ? α
	sin(w+β) ? α

Which is a very easy form to work with.
Labels, statement naming, task begin, etc.

RHT: Terry Winograd points out that labels have a number of uses,
even if GO TO statements are not allowed, since they give you a very
natural way to name a statement.  There are a number of places where
we have been using a string as a tag or label.  This can be somewhat
confusing.

I'd like expand the use of labels, at least on statements, as being
somewhat more convenient, and certainly more conventional.
Presumably, we won't have to declare labels, since the compiler is
essentially multi-pass; so labels will be at least as easy to use.

Also, Terry suggested a better form for prerequiste declarations
inside a task begin, which goes quite nicely with labels.  One
possibility would look something like:

	TASK BEGIN

	S1: INSERT P1 IN H1;
	S2: INSERT P2 IN H2;
	S3: FIT GSK ONTO BODY ... ;
	S4: INSERT HD ONTO BODY ...;

	PREREQUISITES(S3) = S1,S2;
	PREREQUISITES(S4) = S3;

	END;

Another syntax would be

	PREREQUISITES (S3,S1), (S3,S2), (S4,S3);

The basic points are:
	(a) use labels to name statements;
	(b) separate the prerequisite declarations from the
statements themselves.

I pretty much agree with both of these points.  Also, it may be very
desirable to include a number of assertions about the "purposes" of a
given statement or block of statements.

Similarly, Terry suggests that we look very hard at our current
scheme for identifying on-monitors, and other similar constructs.
Thus, we might say

	MON1: ON foo DO <statement>
	 :
	MON2: ON bar DO ENABLE MON1;

This really seems to be somewhat clearer.  We may have already
considered & discarded this approach.  If so, does anyone remember
the reason??

RF -- I agree with use of Labels as stated here.  I have no
feeling about TASKBEGIN syntax.

ODDS & ENDS

TOB -- Lou raised a good point about needing a force and a point to
handle problems like put a record over a spindle.  Perhaps the answer
is torque servo also?

RHT -- Several people (incl TW & RFS) have griped about our use of
the word "ATTACH".  How about using "ASSOCIATE" instead?  Thus, we
might have

	ASSOCIATE F1 TO F2 BY T;
	ASSOCIATE F3 TO F4 AT T1*T2 RIGIDLY; {pornographic}
	 :
	DISASSOCIATE F1 FROM F2;

RF -- What in the world for?
RHT -- "ATTACH" just has too many unfortunate connotations. I really
sort of agree with Terry & Bob about this.  Also, didn't we get the
same comment from several other readers?
RF -- No, we didnt.  I move we use AFFIX and DEFIX, if you really
cant tolerate the much more natural ATTACH, DETACH.  I cannot spell
asossiate.

RHT -- What is the current situation wrt planes?? RFS was wondering
why we just don't use the dual vector (especially since we secretly
use homogeneous coordinates anyhow).  Also, TW was a bit unhappy at
our somewhat special-purpose use of "VECTOR" to mean "three
dimensional vector (whose elements are distances)" -- He suggested
"THREE_VECTOR", or some such, but that seems a bit cumbersome.
RF-- Planes are as stated in the document.  We are only working
in a Euclidean 3-space, so there is no need for any other manner
of vector.  Why should we use the dual vector, and what is it?
RHT -- the point is that a plane and a vector are really the same
thing. As to the 3-d problem: if we ever want to allow vectors to
describe other things than points in space, then the problem becomes real.

RHT -- Any more thoughts on a "clause block", which is
a clause that consists of a whole group of clauses.  The idea came up
in our discussion of compile-time clause variables.

RHT -- Yet another idea from TW: How about some implicit events, like
"Wait for the pegs to all be removed from the box".  The idea is that
the compiler would invent an event variable and then use the world
model to decide where to insert SIGNAL statements.  Seems like a neat
idea, though we don't really need it right away.  Should be easy to
add later, if desired.

RHT -- Is there a "terminate this whole cobegin nest" primitive? Do
we want one?  This seems to be related to the whole problem of
"escape to"- type primitives.
RF -- So far, our philosophy has been that all terminations be
voluntary. It can be quite tricky to force termination of a process
in the act of doing something critical (moving an arm,  updating
database); however,  it is OK to have a flag that is examined once
every interpreter loop and will cause the interpreter to request
termination if it is set.
	We would then need the primitive TERMINATE,  which means what
it says.  Also,  trickier, is TERMINATE <label>.  Most likely need
some scope rule on which labels are accessible to termination.
RHT -- Actually, an "exit this whole nest" primitive would avoid the
need for an explicit TERMINATE statement, at least in this case.
As to underlying runtime structures, I agree that suicide is better
than assasination.

RHT -- If we allow extensible units, perhaps we ought to give some
thought to allowing user-defined tuples.  I'm not sure where that
would be useful, however.
RF -- It is in the class of the "right" thing to do that just isnt
worth the effort for the glory that it would produce.  Like procedure
variables.  Like runtime expressions.  Like English input.
RHT -- I'm not sure it is quite fair to place runtime expressions in
the same class as natural language input.  After all, we already do
have a form of expressions in the graph structures.  
Suggested names for "HAL"

LOU:	HANDY
	COKE	Compiler oriented Konstuction Engine
	ALFA	Assembly language for automation
	FEAT	Factory environment assembly tool
	FEAL	Factory environment assembly language
	tap	totally assinine prospect
	april 	automation programming real-time interactive language
	mumble	must u made bloody language error
|	al	automation language
|	al	automation language
|	al	automation language
|	al	automation language
|	al	automation language
|	al	automation language
|	al	automation language
|	al	automation language
RHT:	HEL	Hand-Eye Language
	SHELL	Stanford Hand Eye Levulose Language
	ANVIL 	Automated Necromancy and Vision Including Language
	SHAPE	Stanford Handeye Assembly Programmable Entity
RF:	LAP	Language for Assembly Programming 
	APL	Assembly Programming Language 
	PAL	Programmable Assembly Language
	FAIL	Factory Assembly Interactive Language
	SAIL	Servoed Assembly Interactive Language
		{RHT: The official version is (or once was)
		      "Suitable Acronym Invented Later" }
	LISP	Language with Interacting Sequential Parts
	FORTRAN	Factory Oriented (Relying on Translation-Orientation
			Analysis) Nemesis
	
	FOAL	Factory Oriented Automation Language
	GOAT	Goal-Oriented Assembly Tasking
	SHALL	Stanford Hardware Automation Lepidopterous Language

RHT:	FOUL	Full Of Ulcers Language
	MANIP	Means of Automating Nearly Impossible Problems
	ARPA	(Assembly Robot Program Automation)

RCB:	SPAS (pronounced "SPAZZ") for Stanford Programmable Assembly System

BES:	HEATHEN	Hand-Eye Assembly Task Highlevel Environment Nodule